Description returns lower bounding time step of a given datetime
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
character(len=*), | intent(in) | :: | fileName | |||
type(DateTime), | intent(in) | :: | given | |||
type(DateTime), | intent(out) | :: | time |
returned time of the grid to sync to |
Type | Visibility | Attributes | Name | Initial | |||
---|---|---|---|---|---|---|---|
character(len=80), | public | :: | attribute | ||||
integer, | public, | DIMENSION(NF90_MAX_VAR_DIMS) | :: | dimIDs | |||
integer(kind=short), | public | :: | i |
loop index |
|||
integer(kind=short), | public | :: | idTime |
Id of the variable containing information on time ccordinate |
|||
integer(kind=short), | public | :: | length |
length of time dimension |
|||
integer(kind=short), | public | :: | nAtts |
number of global attributes |
|||
integer(kind=short), | public | :: | nDims |
number of dimensions |
|||
integer(kind=short), | public | :: | nVars |
number of variables |
|||
integer(kind=short), | public | :: | ncId |
NetCdf Id for the file |
|||
integer(kind=short), | public | :: | ncStatus |
error code return by NetCDF routines |
|||
type(DateTime), | public | :: | refTime |
reference time to calculate time index |
|||
integer, | public | :: | slice(2) | ||||
character(len=19), | public | :: | str | ||||
character(len=80), | public | :: | string | ||||
type(DateTime), | public | :: | timeLower |
lower bound time |
|||
integer, | public | :: | timeSpan | ||||
character(len=30), | public | :: | timeUnit | ||||
type(DateTime), | public | :: | timeUpper |
upper bound time |
|||
character(len=100), | public | :: | variableName |
SUBROUTINE SyncTime & ! (fileName, given, time) USE Units, ONLY: & ! Imported parameters: minute, hour, day, month USE StringManipulation, ONLY: & !Imported routines: ToString IMPLICIT NONE ! Arguments with intent(in): CHARACTER (LEN = *), INTENT (IN) :: fileName TYPE (DateTime), INTENT (IN) :: given ! Arguments with intent out TYPE (DateTime), INTENT (OUT) :: time !!returned time of the grid to sync to !Local variables: INTEGER (KIND = short) :: ncId !!NetCdf Id for the file TYPE (DateTime) :: refTime !!reference time to calculate time index CHARACTER (LEN = 30) :: timeUnit TYPE (DateTime) :: timeLower !!lower bound time TYPE (DateTime) :: timeUpper !!upper bound time !INTEGER (KIND = short) :: next !!index of next time step INTEGER (KIND = short) :: ncStatus !!error code return by NetCDF routines INTEGER (KIND = short) :: nDims !!number of dimensions INTEGER (KIND = short) :: nVars !!number of variables INTEGER (KIND = short) :: nAtts !!number of global attributes INTEGER (KIND = short) :: length !!length of time dimension INTEGER (KIND = short) :: idTime !!Id of the variable containing !!information on time ccordinate CHARACTER (LEN = 80) :: attribute CHARACTER (LEN = 100) :: variableName INTEGER (KIND = short) :: i !!loop index INTEGER :: slice (2) INTEGER :: timeSpan CHARACTER (LEN = 80) :: string CHARACTER (LEN = 19) :: str INTEGER, DIMENSION(NF90_MAX_VAR_DIMS) :: dimIDs !------------end of declaration------------------------------------------------ !open file ncStatus = nf90_open (fileName, NF90_NOWRITE, ncId) IF (ncStatus /= nf90_noerr) THEN CALL Catch ('error', 'GridLib', & TRIM (nf90_strerror (ncStatus) )//': ', & code = ncIOError, argument = fileName ) ENDIF !Read time information CALL ParseTime (ncId, refTime, timeUnit) !inquire dataset to retrieve number of dimensions, variables !and global attributes ncStatus = nf90_inquire(ncId, nDimensions = nDims, & nVariables = nVars, & nAttributes = nAtts ) CALL ncErrorHandler (ncStatus) !search for time variable DO i = 1, nVars attribute = '' ncStatus = nf90_get_att (ncId, varid = i, name = 'standard_name', & values = attribute) IF (ncStatus == nf90_noerr) THEN IF ( attribute(1:4) == 'time' ) THEN idTime = i EXIT END IF ELSE !standard_name is not defined: search for variable named 'time' !ncStatus = nf90_inq_varid (ncId, 'time', varid = i ) ncstatus = nf90_inquire_variable(ncId, varId = i, name = variableName) IF (LEN_TRIM(variableName) == 4 .AND. & variableName(1:4) == 'time' .OR. & LEN_TRIM(variableName) == 5 .AND. & variableName(1:5) == 'Times') THEN !variable 'time' found idTime = i EXIT END IF END IF END DO !inquire time length ncStatus = nf90_inquire_variable(ncid, idTime, dimids = dimIDs) CALL ncErrorHandler (ncStatus) !ncStatus = nf90_inquire_dimension (ncId, dimid = dimIDs(2), len = length) ncStatus = nf90_inquire_dimension (ncId, dimid = dimIDs(1), len = length) CALL ncErrorHandler (ncStatus) DO i = 1, length - 1 !set time step of lower bound slice(1) = i slice(2) = 1 !retrieve date and time ncStatus = nf90_get_var (ncId, idTime, timeSpan , start = slice) CALL ncErrorHandler (ncStatus) SELECT CASE (timeUnit) CASE ('minutes') timeSpan = timeSpan * minute CASE ('hours') timeSpan = timeSpan * hour CASE ('days') timeSpan = timeSpan * day CASE ('months') timeSpan = timeSpan * month END SELECT timeLower = refTime + timeSpan !set time step of upper bound slice(1) = i + 1 slice(2) = 1 !retrieve date and time ncStatus = nf90_get_var (ncId, idTime, timeSpan , start = slice) CALL ncErrorHandler (ncStatus) SELECT CASE (timeUnit) CASE ('minutes') timeSpan = timeSpan * minute CASE ('hours') timeSpan = timeSpan * hour CASE ('days') timeSpan = timeSpan * day CASE ('months') timeSpan = timeSpan * month END SELECT timeUpper = refTime + timeSpan IF ( given == timeLower ) THEN time = timeLower RETURN ELSE IF ( given == timeUpper ) THEN time = timeUpper RETURN ELSE IF ( given > timeLower .AND. given < timeUpper ) THEN time = timeLower RETURN END IF END DO !set next time step !IF (current < length) THEN ! next = current + 1 !ELSE ! next = length !END IF !compute date corresponding to next time step !slice(1) = 1 !slice(2) = next !slice(1) = next !slice(2) = 1 !IF (DateTimeIsDefault(refTime)) THEN ! ncStatus = nf90_get_var (ncId, idTime, str , start = slice) ! CALL ncErrorHandler (ncStatus) ! string = str(1:10) // 'T' // str(12:19) // '+00:00' ! time = string !ELSE ! ncStatus = nf90_get_var (ncId, idTime, timeSpan , start = slice) ! CALL ncErrorHandler (ncStatus) ! SELECT CASE (timeUnit) ! CASE ('minutes') ! timeSpan = timeSpan * minute ! CASE ('hours') ! timeSpan = timeSpan * hour ! CASE ('days') ! timeSpan = timeSpan * day ! CASE ('months') ! timeSpan = timeSpan * month ! END SELECT ! ! time = refTime + timeSpan ! !END IF RETURN END SUBROUTINE SyncTime